A Systematic Translation of Guarded Recursive Data Types to Existential Types

نویسندگان

  • Martin Sulzmann
  • Meng Wang
چکیده

Guarded re ursive data types (GRDT) are a new language feature whi h allows to type he k the di erent bran hes of ase expressions under di erent type assumptions. We show that GRDT an be translated to type lasses with existential types (TCET). The translation to TCET might be problemati in the sense that ommon implementations su h as the Glasgow Haskell Compiler (GHC) fail to a ept the translated program. We establish some suÆ ient onditions under whi h we an provide for a re ned translation from TCET to existential types (ET) based on a novel proof term onstru tion method. The resulting ET program is a epted by GHC. The suÆ ient onditions are met by all GRDT examples we have found in the literature. Our work an be seen as the rst formal investigation to relate the on epts of guarded re ursive data types and (type lasses with) existential types. Categories and Subject Descriptors D.3.2 [Programming Languages℄: Language Classi ations|Appli ative (fun tional) languages; D.3.3 [Programming Languages℄: Language Constru ts and Features|Polymorphism,Constraints; F.3.3 [Logi s and Meanings of Programs℄: Studies of Program Constru ts|Type stru ture General Terms Languages, Theory Keywords Type systems, type-dire ted translation, proof-term onstru tion, onstraint solving. 1. INTRODUCTION Guarded re ursive data types (GRDT) [28℄ introdu ed by Xi, Chen and Chen are a new language feature whi h allows to type he k more programs. The basi idea is to use di erent type assumptions for ea h bran h of a ase expression. E.g., onsider the following (toy) GRDT program. We will use Haskell-style syntax [8℄ throughout the paper. Example 1 We introdu e a GRDT Erk a where a may be re ned depending on the onstru tor. Fun tion f takes advantage of the temporary equality assumptions enabled by pattern mat hing. data Erk a = (a=Int) => I a | forall b.(a=[b℄) => L a f :: Erk a -> a f (I x) = x + 1 f (L x) = tail x In detail, the data type de nition introdu es two onstru tors belonging to data type Erk a. The novelty of GRDT is that in ase of onstru tor I we re ne the type to Erk Int. We present type re nement in terms of equations. In ase of L we re ne the type to Erk [b℄ for some b. Note that GRDT imply existential types [14℄. Constru tor L has type 8a; b:(a = [b℄)) a! Erk a. Therefore, all variables not appearing in the result type are bound by the forall keyword. Note that some presentations [4℄ write I a with (a=Int) instead of (a=Int) => I a. The important point is that when pattern mat hing over values we an make use of these additional type assumptions. Consider the fun tion de nition where in the rst lause we temporarily add a = Int to our assumptions (assuming that x has type a). Thus, we an verify that the x+1 has type a. A similar observation applies to the se ond lause. Hen e, fun tion f is type orre t. 2 GRDT have been re ognized as a very useful language feature, .e.g. onsider [20, 17, 18℄. Hen e, it is desirable to extend existing languages with GRDT. In fa t, a number of authors [1, 2, 3, 27℄ have re ognized that GRDT-style behavior an be expressed in terms of some existing language features already available in Haskell. All of these en odings share the same idea and represent type equalities by Haskell terms. Example 2 Here is an en oding of Example 1 in terms of existential types [14℄. We introdu e a spe ial data typeE a b to represent equality assumption among types. E.g., we represent a = Int by E a Int where the asso iated value E 1 (g,h) implies fun tions g and h to onvert a's to and from Int's. data E a b = E (a->b,b->a) data Erk_H' a = I_H' a (E a Int) | forall b. L_H' a (E a [b℄) f_H' :: Erk_H' a -> a f_H' (I_H' x (E (g,h))) = h ((+) (g x) 1) f_H' (L_H' x (E (g,h))) = h (tail (g x)) Note that we use fun tion notation for addition. Operationally, the onversion fun tions are assumed to represent the identity. Hen e, the above program is equivalent to Example 1. The above program makes only use of existential types and is therefore a epted by GHC [6℄. However, the programmer has to do now more work when de ning the fun tion body. In the rst lause, we turn x into a value of type Int by making use the expli itly provided onversion fun tion g of type a ! Int. Then, we apply (+) whi h is assumed to have type Int ! Int ! Int. Finally, we apply h to obtain a value of type a su h that the type annotation is mat hed. 2 Clearly, su h a style of programming is rather tedious and should be best performed by an automati tool. To the best of our knowledge, we are the rst to propose a systemati translation method from GRDT to ET (existential types) by means of a sour e-to-sour e translation. We see our work as a more prin ipled answer to the many examples we have seen so far in the literature [1, 2, 3, 16, 27℄. The essential task is to onstru t proof terms for type equalities out of logi al statements of the form C t1 = t2 where C onsists of a set of type equations and denotes Boolean impli ation. One of our main te hni al ontribution is a de idable proof term onstru tion method for (dire ted) type equalities. Under the assumption that type assumptions are de omposable we a hieve a translation from GRDT to existential types (ET) whi h is a epted by GHC. In our experien e, the de omposable assumption is satis ed by all GRDT examples we have seen in the literature. We ontinue in Se tion 2 where we introdu e some basi notations. In Se tion 3 we de ne the set of well-typed GRDT programs. Se tion 4 provides for an (intermediate) translation from GRDT to type lasses with existential types (TCET). Se tion 5 provides for a translation s heme from GRDT to ET based on a proof system for type equalities. The translation s heme is omplete if types are de omposable. In Se tion 6 we show that the proof system is deidable. In Se tion 7 we show how to ombine our proof term onstru tion method with a novel inferen e method. Related work is dis ussed in Se tion 8. We on lude in Se tion 9. Due to spa e limitations proofs for all results stated have been moved to the Appendix. 2. PRELIMINARIES We write o to denote a sequen e of obje ts o1; :::; on. We write fv(o) to denote the set of free variables in some obje t o. We assume that the reader is familiar with the on epts of substitution, uni ers, most general uni ers (m.g.u.) et [12℄. E.g., [t=a℄ denotes the substitution whi h has the e e t of repla ing ea h o urren e of a by t. Often, we abbreviate [t1=a1; :::; tn=an℄ by [ t= a℄. We make use of onstraints C onsisting of onjun tion of primitive onstraints su h as t1 = t2 des ribing equality among t1 and t2. We often treat onstraints as sets, therefore, we use \," as a short-hand for Boolean onjun tion. We also assume basi familiarity with rst-order logi . We write j= to denote the model-theoreti entailment relation, to denote Boolean impli ation and $ to denote Boolean equivalen e. We let 9WF denote the formula 9 1 : : : 9 nF where f 1; : : : ; ng = fv(F ) W . We refer to [21℄ for details. 3. GUARDED RECURSIVE DATA TYPES In this se tion, we de ne the set of well-typed GRDT programs. Note that there exist several variations of GRDT su h as Cheney's and Hinze's rstlass phantom types [4℄, Peyton-Jones's, Washburn's and Weiri h's generalized algebrai data types [10℄ and equality-quali ed types by Sheard and Pasali [19℄. Our formulation is losest to the system des ribed by Simonet and Pottier [22℄. First, we de ne the set of expressions and types. Expressions e ::= K j x j x:e j e e j ase e of [pi ! ei℄i2I Patterns p ::= x j (p; p) j K p Types t ::= a j t! t j T t Type S hemes ::= t j 8 :C ) t For simpli ity, we leave out let-de nitions and type annotations but may make use of them in examples. Note that pattern mat hing syntax used in examples an be straightforwardly expressed in terms of ase expressions. GRDT de nitions in example programs su h as data Erk a = (a=Int) => I a | forall b.(a=[b℄) => L a imply onstru tors I : 8a:a = Int ) a ! Erk a and L : 8a; b:a = [b℄) a! Erk a. We prohibit \invalid" de nitions su h as data Unsat a = (a=(a,Int)) => U a whi h yields a onstru tor with an unsatis able set of equations. We assume that booleans, integers, pairs and lists are prede ned. The typing rules des ribing well-typing of GRDT expressions are in Figure 1. We introdu e judgments C; `G e : t to denote that expression e has type t under onstraint C and environment . We assume that C onsists of onjun tion of equations. A judgment is valid if we nd a derivation w.r.t. the typing rules. Note that in we re ord the types of lambda-bound variables and primitive fun tions su h as head : 8a:[a℄ ! a, tail : 8a:[a℄ ! [a℄ et . Rules (Abs), (App) and (Var-x) are standard. Rule (K) seems somewhat redundant and ould be modeled by rules (App) and (Var-x) assuming that onstru tors are re orded in init. Our intention is that onstru tors are always fully applied. Rule (Case) deals with ase expression. Nothing unusual so far. Next, we onsider the GRDT spe i rules. In rule (Eq) we are able to hange the type of an expression. Note that the side ondition C t1 = t2 holds i (1) C does not have a uni er, or (2) for any uni er of C we have 2 (Eq) C; `G e : t C t = t0 C; `G e : t0 (App) C; `G e2 : t2 C; `G e1 : t2 ! t C; `G e1 e2 : t (Abs) C; :x : t1 `G e : t2 C; `G x:e : t1 ! t2 (Var-x) (x : 8 a:t) 2 C; `G x : [ t= a℄t (Case) C; `G e : t1 C; `G pi ! ei : t1 ! t2 for i 2 I C; `G ase e of [pi ! ei℄i2I : t2 (K) K : 8 a; b:D ) t! T a C; `G e : [ t= a; t0= b℄t C [ t= a; t0= b℄D C; `G K e : T t (Pat) p : t1 `G 8 b:(D p) b \ fv(C; ; t2) = ; C ^D; [ p `G e : t2 C; `G p! e : t1 ! t2 (P-Var) x : t `G (True fx : tg) (P-Pair) p1 : t1 `G 8 b1:(D1 p1) p2 : t2 `G 8 b2:(D2 p2) (p1; p2) : (t1; t2) `G 8 b1; b2:(D1 ^D2 p1 [ p1) (P-K) K : 8 a; b:D ) t! T a b \ a = ; p : [ t= a℄t `G 8 b0:(D0 p) K p : T t `G 8 b0; b:(D0 ^ [ t= a℄D p) Figure 1: GRDT Typing Rules that (t1) = (t2) holds. In rule (Pat) we make use of an auxiliary judgment p : t ` 8 b:(D p) whi h establishes a relation among pattern p of type t and the binding p of variables in p. Variables b refer to all \existential" variables. Logi ally, these variables must be onsidered as universally quanti ed. Hen e, we write 8 b. The side ondition b \ fv(C; ; t2) = ; prevents existential variables from esaping. In rule (P-Pair), we assume that there are no name lashes between variables b1 and b2. Constraint D arises from onstru tor uses in p. The other rules are standard. Let's onsider the rst lause of f in Example 1 again. A ording to rule (Pat), the pattern I x provides the additional type assumption a = Int whi h is used in typing of the body x+1. Note that be ause of this additional assumption, rule (Eq) is able to turn the type of x from a to Int. Thus, the expression x+1 is well typed. Similarly, rule (Eq) also turns the type of x+1 to a. Hen e, the annotation given to f is orre t. Rule (Eq) has some other surprising onsequen es. Example 3 Consider the following variation of Example 1 data Erk a = (a=Int) => I a g :: Erk Bool -> b g (I x) = x + 'a' We make use of Bool = Int whi h is equivalent to False to type the body of the lause. Hen e, we an derive anything. Hen e, g has type Erk Bool ! b for any b. Note that we only temporarily make use of False. The onstraint in the nal judgment is satis able. 2 As already observed by Cheney and Hinze [4℄ su h meaningless programs an always be repla ed by \unde ned". Note that we never ever onstru t a value of type Erk Bool. Hen e, w.l.o.g. we slightly restri t the set of typable programs and repla e logi al by onstru tive entailment. Effe tively, we rule out GRDT programs where False o urs in (intermediate) typing judgments. The de nition of onstru tive entailment among type equality is as follows: t = t0 2 C C `= t = t0 C `= t1 = t2 C `= t2 = t3 C `= t1 = t3 C `= t1 = t2 C `= t3 = t4 C `= t1 ! t3 = t2 ! t4 C `= ti = t0i for i = 1; :::; n C `= T t1:::tn = T t01:::t0n We obtain the onstru tive GRDT system `G by repla ing (Eq) with the following rule. (Eq ) C; `G e : t C `= t = t0 C; `G e : t0 Note that Example 3 is not typable anymore in the onstru tive system. 4. TRANSLATING GRDT TO TCET The main result of this se tion is that GRDT an be enoded by type lasses with existential types (TCET). This will form an important intermediate step in our translation to ET. For this purpose, we introdu e a type lass Ct a b to onvert a term of type a into a term of type b. In essen e, we model dire ted equality. The following instan e de larations implement this idea. lass Ct a b where ast :: a->b instan e Ct a a where ast x = x -(Id) instan e (Ct b1 a1, Ct a2 b2) => Ct (a1->a2) (b1->b2) where ast f x = ast (f ( ast x)) -(Arrow) instan e (Ct a1 a2, Ct a2 a3) => Ct a1 a3 where ast a1 = ast ( ast a1) -(Trans) Operationally, the onversion fun tions performs the identity operation for all monomorphi instan es derivable w.r.t. the above rules. 3 We translate GRDT programs to TCET by repla ing ea h equation t1 = t2 in a data type de nition by Ct t1 t2 and Ct t2 t1 Additionally, we apply ast to all sub-expressions. Example 4 Here is the translation of Example 1. data Erk_H a = (Ct a Int, Ct Int a) => I_H a | forall b.(Ct a [b℄, Ct [b℄ a) => L_H a f_H :: Erk_H a -> a f_H (I_H x) = ast (( ast (( ast (+)) ( ast x))) ( ast 1)) f_H (L_H x) = ast (( ast tail) ( ast x)) When typing the se ond lause we temporarily make use of Ct a [b℄ and Ct [b℄ a. Thus, ast x an be given type [b℄. We make use of instan e (Id) to show that ast tail has type [b℄ ! [b℄. Hen e, ( ast tail) ( ast x) has type [b℄. Hen e, ast (( ast tail) ( ast x)) an be given type a. A similar reasoning applies to the rst lause where we make use of instan e (Arrow). Hen e, fun tion f H is type orre t. 2The onne tion between GRDT and TCET be omes obvious when onsidering their underlying formal systems. A formal des ription of TCET overing the single-parameter ase is given by L aufer [13℄. In our own work [23℄, we re ently formalized the general ase in luding multi-parameter type lasses whi h we will make use of in the following. Brie y, in the TCET system we nd now type (multi-paramter) lass onstraints TC t1:::tn instead of equality onstraints t1 = t2. For simpli ity, we assume that instan e de larations are prepro essed and the relations they des ribe are translated to logi formulae. We ommonly denote these logi formulae by Pp and refer to Pp as the program theory. E.g., the instan e de larations from above an be des ribed by the following rst-order formulae. 8a:(Ct a a$ True) 8a1; a2; b1; b2:(Ct (a1 ! a2) (b1 ! b2)$ Ct b1 a1 ^ Ct a2 b2) 8a1; a3:(Ct a1 a3 $ 9a2:(Ct a1 a2 ^ Ct a2 a3) where $ denotes Boolean equivalen e. We refer the interested reader to [24℄ for more details on the translation of instan es to logi formulae. For ea h lass de laration lass TC a1...an where m::t we assume a new primitive m : 8 a:TC a ) t. For simpli ity, we restri t ourselves to monomorphi methods. That is, we require that fv(t) a. Note that the restri tion to monomorphi methods is suÆ ient for the purpose of translating GRDT to TCET. The typing rules for TCET are almost the same as those for GRDT in Figure 1. We adopt rules (App), (Abs), (Var-x), (Case), (Pat), (P-Var), (P-Pair) and (P-K) from Figure 1. However, we drop rule (Eq). Furthermore, we adjust rule (K) and introdu e a new rule (M) to take are of lass methods. (K) K : 8 a; b:D ) t! T a C; `T e : [ t= a℄t Pp j= C [ t= a; t0= b℄D C; `T K e : T t (M) m : 8 a:TC a) t fv(t) a Pp j= C TC t C; `T m : [ t= a℄t Note that entailment is now de ned w.r.t. the program theory. The side ondition Pp j= C [ t= a; t0= b℄D denotes that any model satisfying Pp and C also satis es [ t= a; t0= b℄D. To distinguish the two systems we write C; `T e : t to denote that expression e has type t under onstraint C and environment in the TCET system. In ase of True; `T e : t we sometimes write `T e : t for short. We are in the position to de ne the formal translation from GRDT to TCET. In order to model the onstru tive entailment relation `= among equalities we need to impose some onditions on the program theory. De nition 1 (Full and Faithful) We say that the program theory Pp is full and faithful w.r.t. onstru tive equality i (1) for ea h n-ary type onstru tor T there is some appropriate instan e su h that Pp j= (Ct (T a1:::an) (T b1:::bn) ^ Ct (T b1:::bn) (T a1:::an)) (Ct a1 b1 ^ Ct b1 a1 ^ :::Ct an bn ^ Ct bn an) and (2) all monomorphi ast instan es are equivalent to the identity. Equality among expressions is de ned in terms of a standard denotational semanti s, e.g., onsider [15℄. To turn GRDT typable expressions into TCET typable expressions, we perform a synta ti transformation by applying the ast fun tion to ea h (sub-)expression. We write e[e0℄ to denote a o urren e of e0 in e. De nition 2 (Fully Casted) Let e be an GRDT expression. We onstru t a fully asted expression e0 out of e by applying ast on every subexpression of e. A single transformation step is de ned as e[e1℄ ; e[ ast e1℄ where e1 is synta ti ally di erent from ast e2 for some expression e2. The transformation of GRDT onstru tors is simple. Ea h GRDT onstru tor K : 8 a; b:(t1 = t01; :::; tn = t0n)) t! T a implies a TCET onstru tor K0 : 8 a; b:(Ct t1 t01; Ct t01 t1; :::; Ct tn t0n; Ct t0n tn)) t! T a We an state the following formal onne tion between GRDT and TCET. Theorem 1 (GRDT to TCET) Let e be a GRDT expression and e0 be its fully asted version. For ea h GRDT onstru tor K we introdu e its TCET equivalent K0. Let Pp a full and faithful program theory representing all GRDT type onstru tors mentioned in e. Then, we have that True; `G e : t i True; `T e0 : t. A proof an be found in Appendix B.1. As already pointed out the restri tion to the `G system is not onerous. Note that in order to dire tly translate Example 3 the program theory would need to be strengthened by in luding additional \improvement" rules su h as Pp j= Ct Bool Int False, Pp j= Ct Int Bool False et . The above result is onstru tive in the sense that we an type he k the resulting TCET program if the entire GRDT 4 typing derivation (in luding C `= t1 = t2 derivations) is available. We an also give a meaning to translated TCET program based on the s heme presented in [24℄. However, GHC fails to a ept the TCET program be ause instan e de larations are potentially \non-terminating". 1 E.g., onsider instan e (Trans) from above. When performing ontext redu tion 2 we need to guess the intermediate type when applying instan e (Trans). Hen e, ontext-redu tion may or may not terminate. Hen e, the he k whether C Ct t1 t2 holds where C is a set of Ct assumptions may not terminate. On the other hand, C0 t1 = t2 is de idable assuming that C0 is derived from C by turning ea h Ct t t0 into an equation t = t0. We on lude that we further need to re ne our transformation method for GRDT. The translation to TCET represents an important intermediate step to a hieve a translation to ET whi h is nally a epted by GHC. 5. TRANSLATING GRDT TO ET The result from the previous se tion allows us to assume that GRDT programs have been translated to TCET by fully asting expressions and transforming GRDT onstru tors into TCET onstru tors. Hen e, it is suÆ ient to onsider the translation from TCET to ET. We establish some suÆ ient onditions under whi h we a hieve a type-dire ted translation translation s heme from TCET to ET based on a proof system to onstru t terms onne ted to type lass onstraints Ct t t0. We start o by des ribing our proof system. We assume that onstraints su h as f : Ct a b arry now a proof term f representing \eviden e" for Ct a b. We silently drop f in ase proof terms do not matter. We introdu e judgments of the form f : Ct a b$ F to denote that f is the proof term orresponding to Ct a b under the assumption F where F refers to a (possibly existentially quanti ed) onjun tion of type lass onstraints. The rules des ribing the valid judgments are in Figure 2. Note that we write the a tual de nition of f as part of the premise. Rules (Id), (Var) and (Trans) are straightforward. Rules (Arrow) and (Pair) deal with fun tion and pair types. We assume that the proof rules will be extended a ordingly for user-de ned types. Rule (Æ) allows for the stru tural omposition of proof terms. Rules (8E) and (9E) deal with universal and existential quanti ers. In essen e, we make the onstru tion rules represented by Ct instan e de larations expli it. Example 5 We give the derivation tree for f : Ct a (Int; Bool) $ g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool in Figure 2. For onvenien e, we ombine rule (8E) with rules (Id), (Var), (Arrow). We on lude that f x = let g4 (x,y) = (g2 x,g3 y) in g4 (g1 x) 2 A simple observation of our proof rules shows that the proof system is sound w.r.t. the logi al reading of instan es de larations. 1Indeed, GHC will only a ept instan e (Trans) on e we turn on the \unde idable instan es" option. 2This is the pro ess of resolving type lasses w.r.t. a given set of lass and instan e de larations. Lemma 1 (Soundness) Let Pp be the program theory. Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng su h f : Ct a b $ C is valid. Then, Pp j= C Ct a b. We an also state that proof terms are well-typed. De nition 3 Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng. We onstru t an environment out of C, written as C ; , by mapping ea h g : Ct a b 2 C to g : a! b 2 . Lemma 2 (Well-Typed) Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng and su h that C ; and f : Ct a b $ C is valid. Then ` f : a! b. Proofs an be found in Appendix B.2. Note that the proof term f is equivalent to the identity assuming f1,...,fn are equivalent to the identity as well. As presented, our proof term onstru tion rules in Figure 2 are still non-terminating (see rule (Trans)). In the up oming Se tion 6, we give a de idable pro edure to ompute f : Ct a b$ C given Ct a b and C. We are in the position to systemati ally translate TCET to ET. Ea h TCET onstru tor K : is turned into a ET onstru tor K0 : 0, written (K : ); (K0 : 0). We have that (K : 8 a; b:D ) t ! T a); (K0 : 8 a; b:t ! E t1 t01 ! ::: ! E tn t0n ! T a) whereD = fCt t1 t01; Ct t01 t1; :::; Ct tn t0n; Ct t0n tng. Silently, we assume a xed order among Ct onstraints. Note that the type onstru tor E is de ned in Example 2. For the translation of expressions we introdu e judgments of the form C; `T e : t ; e0 where C holds Ct assumptions, e is a TCET expression and e0 is a ET expression. The translation rules an be found in Figure 3. Our main tasks are to resolve ast fun tions (see rule (Redu e)) based on our proof system and to expli itly insert proof terms in onstru tors (see rule (P-K)). In rule (K), we de ne Pp j= C (g; h) : [ t= a℄D i gi : Ct ti t0i $ C and hi : Ct t0i ti $ C for i = 1; ::; n where [ t= a℄D = fCt t1 t01; Ct t01 t1; :::; Ct tn t0n; Ct t0n tng. Note that Pp j= C (g; h) : [ t= a℄D implies that Pp j= C [ t= a℄D (see Lemma 1). As will see the other dire tion (whi h is ru ial for ompleteness) does not hold ne essarily. We an state soundness of our translation s heme given that the TCET program is typable. Note that the ET system is a spe ial instan e of TCET. We write `E e : t to denote a judgment in the ET system. Theorem 2 (TCET to ET Soundness) Let True; `T e : t and True; `T e : t; e0. Then `E e0 : t. We also nd that e and e0 are equivalent assuming the program theory and proof system is full and faithful. In ombination with Theorem 1 we obtain a systemati translation from GRDT to ET. We do rely on full type information for the GRDT program su h that our proof term onstru tion method is able to insert the appropriate eviden e values. 5 Proof Term Constru tion Rules: (Id) 8a: x:x : Ct a a$ True (Var) 8a; b:f : Ct a b$ f : Ct a b (Trans) f = x:f2 (f1 x) 8a1; a3:f : Ct a1 a3 $ 9a2:f1 : Ct a1 a2; f2 : Ct a2 a3 (Arrow) f = g: x:f2 (g (f1 x)) 8a1; a2; b1; b2:f : Ct (a1 ! a2) (b1 ! b2)$ f1 : Ct b1 a1; f2 : Ct a2 b2 (Pair) f = (x; y):(f1 x; f2 y) C = ff1 : Ct a1 b1; f2 : Ct a2 b2g 8a1; a2; b1; b2:f : Ct (a1; a2) (b1; b2)$ C (Æ) f : Ct a b$ f1 : 1; :::; fn : n fi : i $ Fi F j= Fi for i = 1; :::; n f : Ct a b $ F (8E) 8 a:f : Ct t1 t2 $ F = [ t= a℄ f : Ct (t1) (t2)$ (F ) (9E) f : $ 9a:F f : $ [t=a℄F Example: (Æ) (Trans) f = x:g4 (g1 x) f : Ct a (Int;Bool)$ g1 : Ct a (b; ); g4 : Ct (b; ) (Int; Bool) (Var) g1 : Ct a (b; )$ g1 : Ct a (b; ) (Pair) g4(x; y) = (g2 x; g3 y) g4 : Ct (b; ) (Int; Bool)$ g2 : Ct b Int; g3 : Ct Bool f : Ct a (Int; Bool)$ g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool Figure 2: Proof Term Constru tion Rules and Example Note that we do not obtain ompleteness in general. The problem is that proof terms are not \de omposable" in general. This has already been observed by Chen, Zhu and Xi [2℄. Example 6 Consider data Foo a = K instan e Ct a b => Ct (Foo a) (Foo b) where ast K = K We have that Pp j= g : Ct (Foo a) (Foo b) h : Ct a b but h : Ct a b $ g : Ct (Foo a) (Foo b) does not exist. Hen e, our translation s heme gets possibly stu k in rules (K) and (Redu e). Note that the instan e de laration implies that Ct (Foo a) (Foo b) i Ct a b. The instan e ontext seems somewhat redundant but ne essary to ensure that the program theory models fully and faithfully the entailment relation `= . Clearly, we an build g on type Foo a -> Foo b given h on type a->b whereas for the other dire tion we would need to de ompose proof terms whi h is not possible here. 2 The above is not surprising. Similar situations arise for simple type lass programs. E.g., we annot de ompose Eq [a℄ into Eq a for any a. All what we an do is to identify some suÆ ient onditions whi h allow us to extend the rules in Figure 2 faithfully. De nition 4 (De omposable Types) Let T be a n-ary type onstru tor. We say that T is de omposable at position i where i 2 f1; :::; ng i a proof term onstru tion rule fi : Ct ai bi $ g : Ct (T a1:::an) (T b1:::bn); h : Ct (T b1:::bn) (T a1:::an) exists su h that (1) fi is well-typed under fg : T a1:::an ! T b1:::bn; h : T b1:::bn ! T a1:::ang and (2) fi is equivalent to the identity if g and h are equivalent to the identity. We say that T is de omposable i T is de omposable at all positions. We nd that pairs are de omposable. Example 7 We make use of ? : 8a:a. Consider (Pair1#) g1 = x:fst (f (x;?)) g1 : Ct a1 b1 $ f : Ct (a1; a2) (b1; b2) (Pair2#) g2 = x:snd (f (?; x)) g2 : Ct a2 b2 $ f : Ct (a1; a2) (b1; b2) 2 However, fun tion types seem only to be de omposable in their o-variant position under a non-stri t semanti s. 6 (Abs) C; :x : t1 `T e : t2 ; e0 C; `T x:e : t1 ! t2 ; x:e0 (App) C; `T e2 : t2 ; e02 C; `T e1 : t2 ! t; e01 C; `T e1 e2 : t; e02 e01 (Var-x) (x : 8 a:t) 2 C; `T x : [ t= a℄t; x (Redu e) D C f : Ct t1 t2 $ D C; `T ast : t1 ! t2 ; f (Case) C; `T e : t1 ; e0 C; `T pi ! ei : t1 ! t2 ; p0i ! e0i for i 2 I C; `T ase e of [pi ! ei℄i2I : t2 ; ase e0 of [p0i ! e0i℄i2I (Pat) p : t1 ` 8 b:(D p p0) b \ fv(C; ; t2) = ; C ^D; [ p `T e : t2 ; e0 C; `T p! e : t1 ! t2 ; p0 ! e0 (K) (K : 8 a; b:Ct t1 t01; Ct t01 t1:::; Ct tn t0n; Ct t0n tn ) t! T a) ; (K0 : 8 a; b:t! E t1 t01 ! :::! E tn t0n ! T a) C; `T e : [ t= a℄t; e0 Pp j= C (g; h) : [ t= a℄(Ct t1 t01; Ct t01 t1:::; Ct tn t0n; Ct t0n tn) C; `T Ke : T t; K0 e0 E (g1; h1):::E (gn; hn) (P-Var) x : t ` (True fx : tg x) (P-Pair) p1 : t1 ` 8 b1:(D1 p1 p01) p2 : t2 ` 8 b2:(D2 p2 p02) (p1; p2) : (t1; t2) ` 8 b1; b2:(D1 ^D2 p1 [ p1 (p01; p02)) (P-K) (K : 8 a; b:Ct t1 t01; Ct t01 t1:::; Ct tn t0n; Ct t0n tn ) t! T a) ; (K0 : 8 a; b:t! E t1 t01 ! :::E tn t0n ! T a) b \ a = ; p : [ t= a℄t ` 8 b0:(D0 p p0) g1,h1,...,gn,hn fresh D00 = fD0; g1 : Ct t1 t01; h1 : Ct t01 t1:::; gn : Ct tn t0n; hn : Ct t0n tng K p : T t ` 8 b0; b:(D00 p K0 p0 E (g1; h1):::E (gn; hn)) Figure 3: Type-Dire ted Translation Example 8 (Arrow#) g = x:(f ( y:x)) ? g : Ct a2 b2 $ f : Ct (a1 ! a2) (b1 ! b2) Note that g is the identity under a non-stri t semanti s. However, it seems that h : Ct b1 a1 $ f : Ct (a1 ! a2) (b1 ! b2) does not exist. 2 Example 9 The Either data type is de omposable: data Either a b = Left a | Right b The onstru tion rules are as follow: (EitherL#) g = x:proje tL (f (inje tL x)) g : Ct a1 b1 $ f : Ct (Either a1 a2) (Either b1 b2) (EitherR#) g = x:proje tR (f (inje tR x)) g : Ct a2 b2 $ f : Ct (Either a1 a2) (Either b1 b2) where inje t_L x = Left x proje t_L (left x) = x inje t_R x = Right x proje t_R (Right x) = x Note that the de omposition onditions (De nition 4) are satis ed. Consider the (EitherL#) ase. Expressions are well-typed. Assume f is the identity. Then, f (inje tL x) must yield L x. Hen e, appli ation of proje tL is safe. Hen e, g is the identity. A similar reasoning applies (EitherR#). 2De omposable types ensure that our proof term onstru tion system is not only sound but also omplete. 7 Lemma 3 (De omposition) Let Pp be a full and faithful program theory, Ct t1 t2 a onstraint and C = ff1 : Ct a1 b1; :::; fn : Ct an bng su h that Pp j= C Ct t1 t2 and all types appearing in onstraints are de omposable. Then, f : Ct t1 t2 $ C for some proof term f . The proof is straightforward and pro eeds by indu tion over Pp j= C Ct t1 t2. We are able to state ompleteness of our translation from TCET to ET given that the types appearing in assumption onstraints are de omposable. By assumption onstraints we refer to onstraints D in rule (Pat). Theorem 3 (TCET to ET Completeness) Let True; `T e : t and all types appearing in assumption onstraints in intermediate derivations are de omposable. Then True; `T e : t; e0 for some e0. 6. DECIDABLE PROOF TERM CONSTRUCTION METHOD We introdu e a method to de ide f : Ct t1 t2 $ C (see Figure 2). That is, given C and Ct t1 t2 onstru t a derivation for some f . The main hallenge is to nd a de idable representation for rule (Trans). In the above statement, C ontains the set of Ct assumptions whereas Ct t1 t2 refers to a use site (see rule (Redu e) in Figure 3). In order to distinguish between Ct uses and assumptions we write CtM t1 t2 to refer to a use of Ct. Our task is to onstru t CtM uses out of a given set of Ct assumptions. Note that Ct onstraints an be viewed as dire ted edges. Hen e, the su essful onstru tion of a CtM use is equivalent to nding a path in the graph of Ct edges. However, we do not rely our method on graph algorithms. We would like our method to work even under some additional side onditions su h as CtM t1 t2; CtM t3 t4; t2 = t4 ! a. That is, onstru t CtM t1 t2 and CtM t3 t4 out of some assumption set C under the side ondition that t2 = t4 ! a for some a. Therefore, we view proof term onstru tion as onstraint solving where we rewrite onstraint stores until all CtMs have been resolved. The formal development is as follows. We assume that CtM uses are atta hed to \lo ations". The idea is that i : CtM a b refers to some program text asti where ast is used at type a! b and i refers to the lo ation (e.g., position in the abstra t syntax tree). As before, we write f : Ct a b to refer to the proof term f asso iated to a Ct a b assumption. We employ Constraint Handling Rules (CHRs) [5℄ to onstru t CtM uses out of Ct assumptions. CHRs are a rulebased language for spe ifying transformations among onstraints. A CHR simpli ation rule (R) () d states that if we nd a onstraint mat hing the lhs of a rule we repla e this onstraint by the rhs. We assume that is refer to type lass onstraints and dis refer to either type lass onstraints or equations. Formally, we write C R C 0; ( d) where 2 C su h that ( ) = 0 for some substitution . Silently, we assume the variables in CHRs are renamed before rule appli ation. A CHR propagation rule (R) () d states that if we nd a onstraint mat hing the lhs of a rule we add the rhs to the store. Formally, we write C R C; ( d) where 2 C su h that ( ) = 0. CHRs also have a logi al reading whi h is not relevant here. The CHR-based representation of the proof term onstru tion rules an be found in Figure 4. Note that ea h CHR simpli ation rule also introdu es a transformation rule among expressions written e; e0. We write C D0 to denote an n number of appli ation of CHRs starting with the initial store C yielding store D0. We write e ; e0 to denote a redu tion sequen e among expressions. Proof rules (Arrow) and (Pair) from Figure 2 an be straightforwardly en oded in terms of CHRs. Note that rule (Trans) from Figure 2 has been split into rules (Trans1) and (Id). Our idea is to in rementally build CtM uses out of Ct assumptions. A naive CHR-translation of transitivity su h as (Trans) i : CtM a0 b0 () j : CtM a0 b; k : CtM b b0 astmi ; astmk Æ astmj leads to problems be ause we need to guess b. In CHR terminology, the above CHR is not range-restri ted. We say a CHR is range-restri ted i grounding the lhs grounds the rhs. Note that there is no rule (Var). The same e e t an be a hieved by rule (Trans1) in ombination with rule (Id). Example 10 Here is a sample derivation. We underline onstraints involved in rule appli ations and silently perform equivalen e transformations, repla ing equals by equals. For brevity, we leave out astm transformations. g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; i : CtM a (Int; Bool) Trans1 g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; j : CtM (b; ) (Int; Bool) Pair g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; k : CtM b Int; l : CtM Bool Trans1 g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; m : CtM Int Int; l : CtM Bool Trans1 g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; m : CtM Int Int; n : CtM Bool Bool Id g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool In the above derivation, represents n step derivation. 2There is also another set of rules whi h ex lusively manipulates Ct assumptions. In rule (Trans#) we make use of a CHR propagation rule to build the losure of all available Ct assumptions. Note that we silently avoid to apply propagation rules twi e on the same onstraints (to avoid in nite propagation). Note that for ea h \de omposition" rule we introdu e a propagation rule. The CHR representation of the rules from Example 7 and 8 an be found in Figure 4. It should be lear now that simpli ation rules in rementally resolve CtM uses whereas propagation rules build the losure of all available Ct assumptions. The following example stresses the importan e of propagation rules. 8 CtM Simpli ation Rules: (Id) i : CtM a b () a = b astmi ; x:x (Trans1) g : Ct a b; i : CtM a0 b0 () g : Ct a b; a = a0; j : CtM b b0 astmi ; astmj Æ g (Arrow) i : CtM (a1 ! a2) (b1 ! b2) () i1 : CtM b1 a1; i2 : CtM a2 b2 astmi ; g: x: astmi2 (g ( astmi1 x)) (Pair) i : CtM (a1; a2) (b1; b2) () i1 : CtM a1 b1; i2 : CtM a2 b2 astmi ; (x; y):(( astmi1 x); ( astmi2 y)) Ct Propagation Rules: (Trans#) g : Ct a b; h : Ct b =) h Æ g : Ct a (Pair1#) f : Ct (a1; a2) (b1; b2) =) ( x:fst (f (x;?))) : Ct a1 b1 (Pair2#) f : Ct (a1; a2) (b1; b2) =) ( x:snd (f (?; x))) : Ct a2 b2 (Arrow#) f : Ct (a1 ! a2) (b1 ! b2) =) ( x:(f ( y:x)) ?) : Ct a2 b2 Figure 4: CHR-based Proof Term Constru tion Example 11 Consider g : Ct (b! ) a; h : Ct a (b! d); i : CtM d Trans# g : Ct (b! ) a; h : Ct a (b! d); (h Æ g) : Ct (b! ) (b! d); i : CtM d Arrow# g : Ct (b! ) a; h : Ct a (b! d); (h Æ g) : Ct (b! ) (b! d); ( x:((h Æ g) ( y:x)) ?) : Ct d; i : CtM d g : Ct (b! ) a; h : Ct a (b! d); (h Æ g) : Ct (b! ) (b! d); ( x:((h Æ g) ( y:x)) ?) : Ct d Note that we an only apply (Arrow#) after we have applied (Trans#). 2 Another important observation is that CHRs are \indeterministi ". Example 12 Re all Example 10. We nd the following alternative derivation. g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; i : CtM a (Int; Bool) g1 : Ct a (b; ); g2 : Ct b Int; g3 : Ct Bool; b = Int; = Bool Note that the nal stores di er. Indeed, CHRs are nonon uent. 2 We say a set of CHRs is on uent i any sequen e of derivation steps on the same initial store leads to the same (logi ally equivalent) nal store. In Figure 4 rules (Id) and (Trans1) overlap and therefore we might dis over derivations with same initial store but di erent nal stores. However, we rule out derivations whi h yield \bad" nal stores. Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng and i : CtM a b; C D0. We say that the CHR derivation is good i C and D0 are logi ally equivalent, i.e., j= C $ 9fv(D0) fv(C):D0. That is, we rule out derivations yielding stores with unresolved CtM uses, False and further instantiated Ct assumptions. Note that the derivation in Example 12 is bad be ause the Ct assumptions have been further instantiated in the nal store. We an state that our CHR-based method in Figure 4 is sound w.r.t. the system des ribed in Figure 2. That is, ea h good derivation implies a valid proof. We an also guarantee to nd a good derivation if a proof exists. Furthermore, any good derivation yields equivalent expressions. Lemma 4 (Sound CHR Constru tion) Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng and i : CtM a b; C D0 and astmi ; e su h that the CHR derivation is good. Then, f : Ct a b$ C su h that f and e are equivalent. Lemma 5 (Complete CHR Constru tion) Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng su h that f : Ct a b$ C. Then, i : CtM a b; C C su h that astmi ; e and f and e are equivalent. Lemma 6 (Sound Term Constru tion) Let C = ff1 : Ct a1 b1; :::; fn : Ct an bng, i : CtM a b; C D1 and astmi ; e1 and i : CtM a b; C D2 and astmi ; e2 su h that both CHR derivations are good. Then, e1 and e2 are equivalent. Proofs an be found in Appendix B.5 Note that in order to nd a good derivation we might need to ba k tra k. See Examples 12 and 10. To obtain a deidable proof method we yet need to rule out ertain CHR derivations. E.g., onsider g : Ct a b; h : Ct b a; i : CtM a b Trans1 g : Ct a b; h : Ct b a; j : CtM b b Trans1 g : Ct a b; h : Ct b a; k : CtM a b ::: Fortunately, we are able to rule out su h non-terminating derivations by imposing stronger restri tions on good derivations. The ru ial point is that we disallow \ y li " Ct assumptions of the form g : Ct a (a; b). Su h assumptions must result from invalid GRDT de nitions whi h we generally rule out. Lemma 7 We an impose a omplete termination ondition on good derivations. 9 Details are in Appendix B.6. We on lude that we obtain a de idable CHR-based proof term onstru tion method. Our method is exponential in the worstase. However, we believe that su h ases will rarely appear in pra ti e. An advantage of our method is that we an perform proof term onstru tion under side onditions. This feature allows us to integrate our method with a general solving method for onstru ting typing derivations. Details are dis ussed in the next se tion. 7. COMBING PROOF TERM CONSTRUCTION AND BUILDING TYPING DERIVATIONS Our urrent translation method assumes full type annotations for the GRDT program. Type inferen e for GRDT is a hallenging problem. However, it is mostly suÆ ient to provide annotations for fun tion de nitions only and omit type annotations for sub-expressions. In [23℄, we introdu ed a general type inferen e method for type lasses with existential types. The idea is to generate \impli ation" onstraints out of the program text. Solving of these onstraints allows us to onstru t a typing derivation. The solving proedure for impli ation onstraints is phrased as an extension to CHR solving. Hen e, we an easily ombine the inferen e method introdu ed in [23℄ with our CHR-based proof term onstru tion method. Due to spa e limitations, we explain the approa h by example only. Consider the following TCET program from Example 4. For simpli ity, we only onsider one lause. data Erk H a = forall b.(Ct a [b℄, Ct [b℄ a) => L H a f H :: Erk H a -> a f H (L H x) = ast (( ast tail) ( ast x)) In a rst step, we translate data types and patterns a ording to Figure 3 and repla e all o urren es of ast in the program text by astm where ea h astm o urren es are atta hed to distin t lo ations. data Erk H' a = forall b.L H' a (E a [b℄) f H :: Erk H' a -> a f H (L H' x (E (g,h))) = astm1 (( astm2 tail) ( astm3 x)) A ording to [23℄, we generate the following \impli ation" onstraint out of the above program text. t = Erk a! a; a = Sk1; b = Sk2 a; (g : Ct a [b℄; h : Ct [b℄ a (1 : CtM a1 b1; b1 = a; 2 : CtM a2 b2; a2 = [a02℄! [a02℄; 3 : CtM a3 b3; a3 = a; b2 = b3 ! a1)) (1) Annotation f H::Erk H a->a implies f H::8a:Erk H a! a. Hen e, we substitute a by the skolem onstru tor Sk1. Similarly, we substitute b by Sk2 t. Ea h astmi expression gives rise to i : CtM a b where astmi :: a ! b. To ea h Ct assumption we atta h proof terms (see rule (P-K)). We make use of the TCET representation of GRDT but onne t the onstraints to ET proof terms. The interesting bit is the use of Boolean impli ation to state that under the Ct assumptions we an derive the CtM uses. The onstraint in (1) represents all possible typing derivations. We simply solve this onstraint by applying CHRs de ned in Figure 4 until all CtM uses have been resolved. Thus, all lo ations in the fun tion body referring to proof terms are de ned in terms of proof terms atta hed to Ct assumptions. In general, we solve C0; (D C) by running C0; D D0 and C0; D; C C0 and he k that D0 and C0 are logi ally equivalent (modulo variables in the initial store). We refer the interested reader to [23℄ for more details. For the above onstraint (1) we pro eed as follows. We nd that t = Erk a ! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a (2) is immediately nal.Consider, t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; 1 : CtM a1 b1; b1 = a; 2 : CtM a2 b2; a2 = [a02℄! [a02℄; 3 : CtM a3 b3; a3 = a; b2 = b3 ! a1 f H' (L H' x (E (g,h))) = astm1 (( astm2 tail) ( astm3 x)) $ t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; 1 : CtM a1 a; 2 : CtM ([a02℄! [a02℄) (b3 ! a1); 3 : CtM a b3 ; f H (L H x (E (g,h))) = astm1 (( astm2 tail) ( astm3 x)) Trans1 t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; 1 : CtM a1 a; 2 : CtM ([a02℄! [a02℄) (b3 ! a1); 4 : CtM [b℄ b3 ; f H' (L H' x (E (g,h))) = let astm3 = astm4 Æ g in astm1 (( astm2 tail) ( astm3 x)) Trans1 t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; a1 = [b℄; 5 : CtM a a; 2 : CtM ([a02℄! [a02℄) (b3 ! [b℄); 4 : CtM [b℄ b3 ; f H' (L H' x (E (g,h))) = let astm3 = astm4 Æ g astm1 = astm5 Æ h in astm1 (( astm2 tail) ( astm3 x)) Id t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; (3) b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; a1 = [b℄; ([a02℄! [a02℄) = (b3 ! [b℄); [b℄ = b3 ; f H' (L H' x (E (g,h))) = let astm3 = astm4 Æ g astm1 = astm5 Æ h astm2 x = x astm4 x = x astm5 x = x in astm1 (( astm2 tail) ( astm3 x)) Note that we simultaneously transform onstraints and program text. Constraints involved in rule appli ations are underlined. Silently, we extend e0 ; e00 to e[e0℄; e[e00℄ where e[ ℄ denotes an expression with a hole. For larity, we use let de nitions instead of textually repla ing expressions. Note that nal onstraints (2) and (3) are logi ally equivalent. 10 Hen e, the translation is su essful. Note that the nal program text for the se ond derivation an be simpli ed to the se ond lause in Example 2. We note that several other derivations are possible. E.g., onsider the following where we apply rule (Id) instead of (Trans1). t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; 1 : CtM a1 b1; b1 = a; 2 : CtM a2 b2; a2 = [a02℄! [a02℄; 3 : CtM a3 b3; a3 = a; b2 = b3 ! a1 $ t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; 1 : CtM a1 a; 2 : CtM ([a02℄! [a02℄) (b3 ! a1); 3 : CtM a b3 Id t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; a = b3; 1 : CtM a1 a; 2 : CtM ([a02℄! [a02℄) (a! a1) Id t = Erk a! a; a = Sk1; b = Sk2 a; g : Ct a [b℄; h : Ct [b℄ a; b1 = a; a2 = [a02℄! [a02℄; a3 = a; b2 = b3 ! a1; a = b3; ([a02℄! [a02℄) = (a! a1) 1 : CtM a1 a $ False Note that skolem variable Sk1 is uni ed with [a02℄ whi h immediately yields failure. That is, we obtain a \bad" nal store (see Appendix B.6 for details). However, there might be other derivations whi h yield \good" nal stores. Ea h of them orresponds to a valid solution and all of them are equivalent (see Lemma 6). The following is another possible translation of Example 2. f H' (L H' x (E (g,h))) = let astm2 g x = astm5 (g ( astm4 x)) astm4 = g astm5 = h astm1 x = x astm3 x = x in astm1 (( astm2 tail) ( astm3 x)) 8. RELATED WORKOur systemati translation method is inspired by the workby Baars and Swierstra [1℄, Chen, Zhu and Xi [2℄, Hinzeand Cheney [3℄. These works showed by example how to ex-press GRDT-style behavior by representing type equalitiesby Haskell terms and insert appropriate onversion fun -tions into the program text. We note that none of theseworks onsiders a systemati translation s heme.Note that in [1, 3, 16℄ equality is represented in terms of thefollowing de nition.newtype EQ a b = EQ (forall f. f a->f b)The above en odes Leibnitz' law whi h states that if a andb are equivalent then we may substitute one for the other inany ontext. By onstru tion this ensures that the only in-habitant of EQ a b is the identity (ex luding non-terminatingfun tions whi h might break this property). Our represen-tation of equality makes it ne essary to postulate that allvalues atta hed to monomorphi instan es of E t t repre-sent the identity to ensure preservation of the semanti s ofprograms (see De nition 1). On the other hand, the EQ rep-resentation fa es problems when trying to manipulate proofterms. E.g., there are situations where we need to \de om-pose" a value of type EQ (a,b) ( ,d) into a value of typeEQ a whi h is impossible based on the above de nition.Example 6 shows that our representation of type equalityshares the same problem. However, we believe that our rep-resentation is more likely to be de omposable.Weiri h [27℄ also onsidered a type lass en oding based onsingle-parameter type lasses. Our use of multi-parametertype lasses in ombination with extential types appears tobe novel and more natural to mimi GRDT-style behavior.Kiselyov [11℄ suggests an alternative type lass en oding ofGRDT. The gist of his idea is to turn ea h (value) patternlause into an (type lass) instan e de laration. We believethat in addition to the already \problemati " instan e de -laration for transitivity su h an en oding s heme may reatefurther potentially non-terminating instan es. We are notaware of any formal results whi h mat h the results statedin this paper.Pottier and Gauthier [17℄ give a type-preserving defun tion-alization of polymorphi programs to System F extendedwith GRDT. Their formal results (proofs of Lemmas 4.1 and4.2 in [17℄) let us onje ture that resulting GRDT programsan be translated to ET based on our translation method.Our proof term onstru tion method an be seen as a re nedversion of the type-dire ted eviden e-translation s heme [7℄for Haskell. We ould a hieve a de idable onstru tion fora seemingly non-terminating set of instan es. There aresome onne tions to methods for nding paths in graphs and\ask" onstraints whi h appear in the ontext of onstraint-logi programming [9℄. We yet need to work out the exa tdetails.9. CONCLUSIONThe primary goal of our work was to on isely study and re-late the on epts of guarded re ursive data types (GRDT),existential types (ET) and type lasses (TCET). We oulda hieve this goal by giving for the rst time a systematitranslation method from GRDT to ET (Se tion 5) based onan intermediate translation to TCET (Se tion 4). For thetranslation method to be omplete we require that typesappearing in assumption onstraints must be de omposable(De nition 4). We also assume full GRDT type informa-tion but are able to onstru t ET expressions automati-ally based on a novel CHR-based proof term onstru tionmethod (Se tion 6). We an even ombine our methodwith an independently developed type inferen e s heme forGRDT (Se tion 7). Hen e, we obtain a fully automati toolto translate GRDT to ET where the nal program is a -epted by GHC. In our experien e, the de omposition on-dition whi h is ru ial for translation is met by all GRDTexamples found in the literature. A omprehensive list ofexamples an be found under 3http://www. omp.nus.edu.sg/~wangmeng/trans-grdtAn issue we yet need to investigate is how expensive proofterm manipulations are in pra ti e. Note that onversionfun tions represent the identity, however, we may have to3Examples are also part of the te hni al report version [25℄.11 repeatedly apply su h fun tions to elements of lists et . A\smart" ompiler may be able to avoid su h redundant om-putations (either stati ally or dynami ally). In this ontext,we would like to mention that GRDT have been re entlyadded to Haskell. Implementations are available in the lat-est release of GHC [6℄ and Chameleon [26℄ (experimentalversion of Haskell). In ase of GHC, the Core ba k-end hasbeen extended with GRDT as a primitive feature. Clearly,we expe t \native" GRDT ode to run faster than \sour e-to-sour e translated" GRDT ode. However, the advantageof our work is that we ould identify a large lass of GRDTprograms whi h an be implemented by a sour e-to-sour etranslation. Thus, our work o ers a light-weight approa hto write GRDT-style programs based on some existing lan-guage features.Our proof term onstru tion method is of independent in-terest and my prove to be useful to advan e the state of artin type-dire ted translations for languages su h as Haskell.This is another interesting avenue whi h we plan to explorein the future.AcknowledgementsWe thank Gregory Du k, Simon Peyton-Jones and JeremyWazny for their omments. In parti ular, we would like tothank James Cheney and Oleg Kiselyov for fruitful dis us-sions.10. REFERENCES[1℄ A. I. Baars and S. D. Swierstra. Typing dynamityping. In Pro . of ICF'02, pages 157{166. ACMPress, 2002.[2℄ C. Chen, D. Zhu, and H. Xi. Implementing utelimination: A ase study of simulating dependenttypes in Haskell. In Pro . of PADL'04, volume 3057 ofLNCS, pages 239{254. Springer-Verlag, 2004.[3℄ J. Cheney and R. Hinze. A lightweightimplementation of generi s and dynami s. In Pro . ofHaskell Workshop'02, pages 90{104. ACM Press, 2002.[4℄ J. Cheney and R. Hinze. Firstlass phantom types.Te hni al Report CUCIS TR2003-1901, CornellUniversity, 2003.[5℄ T. Fruhwirth. Constraint handling rules. In ConstraintProgramming: Basi s and Trends, LNCS.Springer-Verlag, 1995.[6℄ Glasgow haskell ompiler home page.http://www.haskell.org/gh /.[7℄ C. V. Hall, K. Hammond, S. Peyton Jones, andP. Wadler. Type lasses in Haskell. In ESOP'94,volume 788 of LNCS, pages 241{256. Springer-Verlag,April 1994.[8℄ Haskell 98 language report.http://resear h.mi rosoft. om/Users/simonpj/haskell98-revised/haskell98-report-html/.[9℄ Joxan Ja ar and Mi hael Maher. Constraint logiprogramming: A survey. Journal of LogiProgramming, 19(20):503{581, 1994.[10℄ S. Peyton Jones, G. Washburn, and S. Weiri h.Wobbly types: type inferen e for generalised algebraidata types, 2004. Submitted to POPL'05.[11℄ O. Kiselyov. Typed lambda-expressions without gadts.http://www.haskell.org//pipermail/haskellafe/2005-January/008212.html, 2005. Haskell-Cafe MailingList.[12℄ J. Lassez, M. Maher, and K. Marriott. Uni ationrevisited. In Foundations of Dedu tive Databases andLogi Programming. Morgan Kau man, 1987.[13℄ K. Laufer. Type lasses with existential types. Journalof Fun tional Programming, 6(3):485{517, 1996.[14℄ K. Laufer and M. Odersky. An extension of ML withrstlass abstra t types. In ACM SIGPLANWorkshop on ML and its Appli ations, pages 78{91,1992.[15℄ D. Ma Queen, G. Plotkin, and R. Sethi. An idealmodel for re ursive polymorphi types. Informationand Control, 71:95{130, 1986.[16℄ E. Pasali . The Role of Type Equality inMeta-Programming. PhD thesis, Oregon Health &S ien e University, OGI S hool of S ien e &Engineering, September 2004.[17℄ F. Pottier and N. Gauthier. Polymorphi typeddefun tionalization. In Pro . of POPL'04, pages89{98. ACM Press, January 2004.[18℄ Franois Pottier and Yann Rgis-Gianas. TowardseÆ ient, typed LR parsers. Draft paper, September2004.[19℄ T. Sheard and E. Pasali . Meta-programming withbuilt-in type equality. In Fourth InternationalWorkshop on Logi al Frameworks andMeta-Languages, 2004.[20℄ Tim Sheard. Languages of the future. SIGPLAN Not.,39(10):116{119, 2004.[21℄ J.R. Shoen eld. Mathemati al Logi . Addison-Wesley,1967.[22℄ V. Simonet and F. Pottier. Constraint-based typeinferen e with guarded algebrai data types.Submitted to ACM Transa tions on ProgrammingLanguages and Systems, June 2004.[23℄ P. J. Stu key and M. Sulzmann. A unifying inferen eframework for Hindley/Milner with extensions.http://www. omp.nus.edu.sg/~ sulzmann, 2004.[24℄ P.J. Stu key and M. Sulzmann. A theory ofoverloading. ACM Transa tions on ProgrammingLanguages and Systems, 2004. To appear.[25℄ M. Sulzmann and M. Wang. A systemati translationof guarded re ursive data types to existential types.Te hni al Report TR22/04, The National Universityof Singapore, 2004.[26℄ M. Sulzmann and J. Wazny. Chameleon.http://www. omp.nus.edu.sg/~ sulzmann/ hameleon.[27℄ S. Weiri h. Type-safe ast: (fun tional pearl). In Pro .of ICFP'00, pages 58{67. ACM Press, 2000.[28℄ H. Xi, C. Chen, and G. Chen. Guarded re ursivedatatype onstru tors. In Pro . of POPL'03, pages224{235. ACM Press, 2003.12 APPENDIXA. SEMANTICS OF EXPRESSIONSWe follow the ideal semanti s of Ma Queen, Plotkin andSethi [15℄. The meaning of a term is a value in the CPO V,where V ontains all ontinuous fun tions from V to V andan error elementW, usually pronoun ed \wrong". Depend-ing on the on rete type system used, V might ontain otherelements as well. We assume that the values of additionaltype onstru tors are representable in the CPO V. Then Vis the least solution of the equationV = W? + V ! V:The meaning fun tion on terms is as follows:[[x℄℄= (x)[[ u:e℄℄ = v:[[e℄℄ [u := v℄[[e e0℄℄ = if [[e℄℄ 2 V ! V ^ [[e0℄℄ 6=Wthen ([[e℄℄ ) ([[e0℄℄ )elseW[[letx = e in e0℄℄ = if [[e℄℄ 6=Wthen [[e0℄℄ [x := [[e℄℄ ℄elseWNote that the above semanti s is all{by value.B. PROOFSB.1 Proof of Theorem 1 (GRDT to TCET)First, we introdu e a auxilliary de nition and lemma to es-tablish a onne tion between onstru tive type equality en-tailment and entailment among type lasses.De nition 5 Let C be a set of term equality onstraintsand C0 be a set of type lass onstraints. We say that Cis equivalent to C0, written as C C0, i (8t t0:t = t0 2C i (Ct t t0 2 C0 ^ Ct t0 t 2 C0)).We all C0 the \Ct"equivalent of C; and C the \Eq" equivalent of C0.Lemma 8 Let Pp be a full and faithful type lass theory. LetC be a set of equality onstraints and C0 its \Ct" equivalent.We have C `= t1 = t2 i Pp j= C0 (Ct t1 t2; Ct t2 t1).Proof. The proof is done in two dire tions. (Dire tion )): We proof by indu tion on derivations.Æ Case:t = t0 2 CC `= t = t0Be ause we have t = t0 2 C, we know Ct t t0 2 C0 andCt t0 t 2 C0. Thus Pp j= C0 (Ct t t0; Ct t0 t).Æ Case:C `= t1 = t2 C `= t2 = t3C `= t1 = t3By indu tion, we havePp j= C0 (Ct t1 t2; Ct t2 t1; Ct t2 t3; Ct t3 t2)By the type lass instan e8a1; a3:(Ct a1 a3 $ 9a2:(Ct a1 a2 ^ Ct a2 a3))We on ludePp j= C0 (Ct t1 t2; Ct t2 t1; Ct t2 t3; Ct t3 t2)(Ct t1 t3; Ct t3 t1)Other ases are similar.(Dire tion ():Æ Case: Suppose the type lass instan e8a:(Ct a a$ True)is applied. Then we havePp j= True Ct t tWe also haveTrue `= t = tÆ Case: Suppose the type lass instan e8a1; a3:(Ct a1 a3 $ 9a2:(Ct a1 a2 ^ Ct a2 a3))is applied. Then we havePp j= 9t2:(Ct t1 t2 ^ Ct t2 t3) Ct t1 t3Easily, we also obtaint1 = t2 ^ t2 = t3 `= t1 = t3Other ases are similar.The next lemma follows immediately from the rule (M).Lemma 9 C; `T ast : t! t0 i Pp j= C Ct t t0We obtain Theorem 1 as a spe ial instan e from the follow-ing lemma.Lemma 10 Let e be a GRDT expression and e0 be its fullyasted version. Let Pp a full and faithful program theoryrepresenting all GRDT type onstru tors mentioned in e.Silently, we transform the GRDT onstru tors mentionedin e to TCET onstru tors. We have that C; `G e : t iC0; `T e0 : t where C0 is the \Ct" equivalent of C.Proof. The proof is done in two dire tions.(Dire tion )):We proof by indu tion on derivation.Æ Case (Eq): C; `G e : t C `= t = t0C; `G e : t0By the indu tion hypothesis, we haveC0; `T e0 : t (1)13 Also by Lemma 8 and C `= t = t0 we havePp j= C0 (Ct t t0; Ct t0 t) (2)From (1) and (2), we on lude thatC0; `T ( ast e0) : t0W.l.o.g. We an assume e0 ( ast e00). Thus we obtainC0; `T (( ast Æ ast) e00) : t0We assume C0; `T e00 : t00. In the above ase, the rst astis of type t! t0 and the se ond t00 ! t. Thus by Lemma 9,we know that Ct t t0 and Ct t00 t an be derived from theontext. By the (Trans) type lass instan e, we an deriveCt t00 t0. Then by Lemma 9, we know there exists a ast oftype t00 ! t0. After repla ing the ast omposition astÆ astin the above judgement by the new ast, we obtainC0; `T ( ast e00) : t0This is equivalent to C0; `T e0 : t0Æ Case (App):C; `G e1 : t2 ! t C; `G e2 : t2C; `G e1 e2 : tBy the indu tion hypothesis, we haveC0; `T e01 : t2 ! t C0; `T e02 : t2By appli ation of rule (App), we obtainC0; `T (e01 e02) : t (1)Note that we always have C `= t = t. Thus we on ludeC0; `T ( ast(e01 e02)) : tOther ases are similar.(Dire tion (): We pro eed by stru tural indu tion. Wedenote by [[e0℄℄ the \erasure" of expression e0, i.e. we eraseall ast o urren es from e0. W.l.o.g. We an assume e0( ast e00).Æ e00 = x C0; `T ast : t! t0 C0; `T e00 : tC0; `T ( ast e00) : t0Be ause e00 = x, then [[e00℄℄ = e00. Therefore, we haveC; `G [[e00℄℄ : t (1)By C0; `T ast : t! t0 and Lemma 9, we obtainPp j= C0 (Ct t t0; Ct t0 t)Together with Lemma 8, we haveC `= t = t0 (2)By (1), (2) and rule (Eq), we on ludeC; `G [[e00℄℄ : t0Be ause [[ ast e00℄℄ = [[e00℄℄, then we haveC; `G [[ ast e00℄℄ : t0This is equivalent to C; `G [[e0℄℄ : t0Æ e00 = x:e000C0; `T ast : t! t0 C0; :x : t1 `T e000 : t2C0; `T e00 : tC0; `T ( ast e00) : t0In the above derivation t = t1 ! t2. By the indu tionhypothesis, we haveC; :x : t1 `G [[e000℄℄ : t2By applying the (Abs) rule, we obtainC; `G [[e00℄℄ : t (1)By C0; `T ast : t! t0 and Lemma 9, we obtainPp j= C0 (Ct t t0; Ct t0 t)Together with Lemma 8, we haveC `= t = t0 (2)By (1), (2) and rule (Eq), we on ludeC; `G [[e00℄℄ : t0Be ause [[ ast e00℄℄ = [[e00℄℄, then we haveC; `G [[ ast e00℄℄ : t0This is equivalent to C; `G [[e0℄℄ : t0Æ e00 = (e0001 e0002 )C0; `T Ct : t! t0 C0; `T e0001 : t2 ! t C0; `T e000 : t2C0; `T e00 : tC0; `T (Ct e00) : t0By the indu tion hypothesis, we haveC; `G [[e0001 ℄℄ : t2 ! tC; `G [[e0002 ℄℄ : t2By applying the (App) rule, we obtainC; `G [[[[e0001 ℄℄ [[e0002 ℄℄℄℄ : t (1)By C0; `T ast : t! t0 and Lemma 9, we obtainPp j= C0 (Ct t t0; Ct t0 t)Together with Lemma 8, we haveC `= t = t0 (2)By (1) and (2), we on ludeC; `G [[e00℄℄ : t0Be ause [[ ast e00℄℄ = [[e00℄℄, then we haveC; `G [[ ast e00℄℄ : t0This is equivalent to C; `G [[e0℄℄ : t0Other ases are similar.14 B.2 Proof of Lemma 2 (Well-Typed)Our assumptions are: Let C = ff1 : Ct a1 b1; :::; fn :Ct an bng and su h that C ; and f : Ct a b $ Cis valid. Then ` f : a! b.Proof. The proof pro eeds by indu tion over the proofterm onstru tion derivation. W.l.o.g we ombine rule (8 E)with rules (Id),(Var),(Arrow) et. We also ombine (9 E)with (Trans).Æ Case(Id):x:x : Ct a a$ TrueWe know that = ;. Thus we on lude ` x:x : a! a.Æ Case (Var): f : Ct a b$ f : Ct a bWe know that = ff : a ! bg. Thus we on lude ` f :a! b.Æ Case (Trans): f = g: x:f2 (g (f1 x))f : Ct a1 a3 $ f1 : Ct a1 a2; f2 : Ct a2 a3We know that = ff1 : a1 ! a2; f2 : a2 ! a3g. Thus bytyping derivation we an easily on lude ` f : a1 ! a3.Æ Case (Arrow): Similar to (Trans).Æ Case (Æ):f : Ct a b$ f1 : 1; :::; fn : n fi : i $ FiF j= Fi for i = 1; :::; nf : Ct a b$ FBy indu tion, we haveSn1 i ` f : a! b. Be auseSn1 iderived from F j= Fi, then we on lude ` f : a! b. B.3 Proof of Theorem 2 (TCET to ET Sound-ness)Theorem 2 follows dire tly from the following more generallemma.Lemma 11 Let C; `T e : t, C; `T e : t ; e0 and0su h that C ; 0. Then [ 0 `E e0 : t.Proof. The proof pro eeds by indu tion on derivations.Æ Case (K):(K : 8a; b:Ct t1t01; Ctt01 t1:::; Ct tnt0n; Ctt0n tn ) t! T a);(K0 : 8a; b:t! E t1t01 ! :::! E tnt0n ! T a)C; `T e : [ t=a℄t; e0Pp j= C (g; h) : [ t=a℄(Ct t1t01; Ctt01 t1:::; Ct tnt0n; Ctt0n tn)C; `T Ke : T t; K0 e0 E (g1; h1):::(gn; hn)By the indu tion hypothesis, we have[ 0 `E e0 : [t=a℄t (1)Also we haveK0 : 8a; b:t! E t1t01 ! ::: ! E tnt0n ! T a (2)Note that here we assume an ordering among the onstraints.Pp j= C (g; h) : [ t=a℄(Ct t1t01; Ctt01 t1:::; Ct tnt0n; Ctt0n tn)implies gi : Ct tit0i $ C and hi : Ctt0i ti $ CW.l.o.g we an assume gi; hi =2 . Hen e by Lemma 2, wehave [ 0 `E gi : ti !t0i and [ 0 `E hi :t0i ! tiwhere i = 1 : : : nThus we an obtain that[ 0 `E E (gi; hi) : E tit0i where i = 1 : : : n (3)From (1),(2),(3) and rule (K), we on lude[ 0 `E K0 e0 E (g1; h1):::(gn; hn) : T tÆ Case (Redu e):D C f : Ct t1 t2 $ DC; `T ast : t1 ! t2 ; fGiven D C f : Ct t1 t2 $ D, W.l.o.g. we assume f =2 .Thus we on lude by Lemma 2[ 0 `E f : t1 ! t2Æ Case (Pat):p : t1 ` 8 b:(D p p0) b \ fv(C; ; t2) = ;C ^D; [ p `T e : t2 ; e0C; `T p! e : t1 ! t2 ; p0 ! e0By the indu tion hypothesis, we have[ p [ C [ D `T e0 : t2where C ; C and D ; D.Also by Lemma 12 (see below), we have p0 ` 8 b:( p [ D).Thus we on lude[ C `E p0 ! e0 : t1 ! t2Æ Other ases are standard.Lemma 12 Given p : t1 ` 8 b:(D p p0) then p0 ` 8 b: p[0 where D; 0.Proof. Standard by indu tion on derivation.15 B.4 Proof of Theorem 3 (TCET to ET Com-pleteness)Theorem 3 follows dire tly from the following lemma.Lemma 13 Let C; `T e : t and all types appearing inassumption onstraints in intermediate derivations are de-omposable. The C; `T e : t; e0 for some e0.Proof. The proof is done by onstru tion of e0.Æ Case (Redu e):Note that ast is a lass method of type 8t; t0:Ct t t0 ) t!t0. Sin e we have C; `T ast : t1 ! t2, by rule (M), wean derive Pp ` C Ct t1 t2.Given all the types are de omposable, by Lemma 3, we knowf : Ct t1 t2 $ C for some f if Pp ` C Ct t1 t2. Thus therule (Redu e) always produ es a f .Æ Case:Other rules are standard. B.5 Proofs of Lemmas 4, 5 and 6B.5.1 Proof of Lemma 4 (Sound CHR Construction)Our assumptions are: Let C = ff1 : Ct a1 b1; :::; fn :Ct an bng and i : CtM a b; CD0 and astmi ; e su hthat the CHR derivation is good. Then, f : Ct a b $ Csu h that f and e are equivalent.Proof. The proof is done through indu tion on the CHRderivation. W.l.o.g we ombine rule (8 E) with rules (Id),(Var), (Arrow) and (Pair). We also ombine (9 E) with(Trans).Æ Suppose the rule applied is (Id):i : CtM a b; Ca = b; CD0astmi ; x:xNote that the above derivation uni es a and b. Thus wehavex:x : Ct a a$ True:Æ Suppose the rule applied is (Trans1):i : CtM a b; Cag = a; j : CtM bg b; CD0astmi ; astmj Æ gNote that the above derivation uni es a and ag. Thus wehave(Æ) (Trans)f = astmj Æ gf : Ct a b$ g : Ct a bg; astmj : Ct bg bf : Ct a b$ Dwhere g : Ct a bg C. Also by indu tion, we knowj : Ct bg b $ D0 for some D0 C. Take D as D0, wehave D C.Æ Suppose the rule applied is (Arrow):i : CtM (a1 ! a2) (b1 ! b2); Ci1 : CtM b1 a1;i2 : CtM a2 b2; CD0astmi ; g: x:astmi2(g ( astmi1 x))Also we have(Æ) (Trans)f = g: x: astmi2(g ( astmi1 x))f : Ct (a1 ! a2) (b1 ! b2)$ astmi1 : Ct b1 a1;astmi2 : Ct a2 b2f : Ct (a1 ! a2) (b1 ! b2)$ DAlso by indu tion, we know j : Ct b1 a1 $ D0 and j :Ct a2 b2 $ D00for some D0 C and D00 C. Take D asD0 [D00, we have D C.Æ (Pair) is similar to (Arrow). B.5.2 Proof of Lemma 5 (Complete CHR Construc-tion)Our assumptions are: Let C = ff1 : Ct a1 b1; :::; fn :Ct an bng su h that f : Ct a b$ C. Then, i : CtM a b; CC su h that astmi ; e and f and e are equivalent.Proof. W.l.o.g we ombine rule (8 E) with rules (Id),(Var), (Arrow) and (Pair). We also ombine (9 E) with(Trans).Æ Case (Id).x:x : Ct a a$ TrueThen we havei : CtM a a;CId a = a; Castmi ; x:xÆ Case (Var).f : Ct a b$ f : Ct a bThen we have, given f : Ct a b 2 Ci : CtM a b; CTrans1 j : CtM b b; CId Castmi ;astmi Æ f ; x:x Æ fÆ Case (Trans).(Trans)f = x:f2 (f1 x)f : Ct a1 a3 $ f1 : Ct a1 a2; f2 : Ct a2 a3We havei : CtM a1 a3; f1 : Ct a1 a2; f2 : Ct a2 a3astmiTrans1 j : Ct a2 a3; f1 : Ct a1 a2; f2 : Ct a2 a3;astmj Æ f1Trans1 k : CtM a3 a3; f1 : Ct a1 a2; f2 : Ct a2 a3;astmk Æ f2 Æ f1Idf2 Æ f1 : Ct a1 a2; f2 : Ct a2 a3;x:x Æ f2 Æ f1Æ Case (Arrow).(Arrow)f = g: x:f2 (g (f1 x))8a1; a2; b1; b2:f : Ct (a1 ! a2) (b1 ! b2)$ f1 : Ct b1 a1; f2 : Ct a2 b216 By indu tion, C; i1 : CtM b1 a1D1astmi1; f1C; i2 : CtM a2 b3D2astmi2; f2Therefore i : CtM (a1 ! a2) (b1 ! b2); f1 : Ct b1 a1;f2 : Ct a2 b2astmiArrow i1 : CtM b1 a1; i2 : CtM a2 b2; f1 : Ct b1 a1;f2 : Ct a2 b2;g: x: astmi2 (g ( astmi1 x))V ar f1 : Ct b1 a1; f2 : Ct a2 b2;g: x:f2 (g (f1 x))Æ (Pair) is similar to (Arrow). B.5.3 Proof of Lemma 6 (Sound Term Construction)Our assumptions are: Let C = ff1 : Ct a1 b1; :::; fn :Ct an bng, i : CtM a b; CD1 and astmi ; e1 andi : CtM a b; CD2 and astmi ; e2 su h that bothCHR derivations are good. Then, e1 and e2 are equivalent.Proof. Let f : Ct a b $ C, from Lemma 4, we knowthat e1 is equivalent to f and e2 is equivalent to f . Thus weon lude that e1 is equivalent to e2.B.6 Termination of CHRsWe impose a termination ondition on derivations. We showthat this ondition does not rule out any good derivationswhi h are vital. The basi idea is to atta h ea h onstraintwith a distin t justi ation. Justi ations J refer to sets ofnumbers. Ea h Ct onstraints arries a distin t, singletonjusti ations sets. Ea h CtM onstraints arries initially asingleton justi ation set referring to its lo ation. We writej as a short-hand for the singleton set fjg. We need tomaintain justi ations during CHR appli ations.Consider rule instan e (Trans1) g : Ct a b; i : CtM a0 b0 ()g : Ct a b; a = a0; j : CtM b b0 and store C su h that(g : Ct a b)j ; (i : CtM a0 b0)J 2 C Then C Trans1 C (i :CtM a0 b0)J ; a = a0; (j : CtM bb0)fjg[J . We say that thetermination ondition is violated i j 2 J .Consider rule instan e (Arrow) i : CtM (a1 ! a2) (b1 !b2) () i1 : CtM b1 a1; i2 : CtM a2 b2 su h that (i :CtM (a1 ! a2) (b1 ! b2))J 2 C. Then, C Arrow C(i : CtM (a1 ! a2) (b1 ! b2))J ; (i1 : CtM b1 a1)J ; (i2 :CtM a2 b2)J . The justi ed CHR semanti s for rule (Pair)is similar.Silently, we assume that all propagation rules have been ex-haustively applied su h that all Ct onstraints are atta hedwith a unique number. Note that we ould en ounter \dupli-ates" su h as (g1 : Ct a b)j1 and (g2 : Ct a b)j2 . However, g1and g2 are equivalent. Hen e, we may keep both onstraints.We impose an order among derivations. Let C = ff1 :Ct a1 b1; :::; fn : Ct an bng, i : CtM a b; CD1 andastmi ; e1 and i : CtM a b; CD2 and astmi ; e2su h that both CHR derivations are good. We say thati : CtM a b; CD1 is shorter than i : CtM a b; CD2 i the size of e1 is shorter than the size of e2 wherethe size fun tion returns the number of nodes in the syntaxtree of an expression. In ase of initial stores with multipleCtMs we ompare the sum of the individual sizes of resultingexpressions.Lemma 14 Let i : CtM t t;CD be a good derivation.Then, astmi ; e where e is equivalent to the identity.Lemma 15 Any good derivation whi h violates the termi-nation ondition an be shortened.Proof. We assume a good derivation whi h violates thetermination ondition where we onsider the \earliest" vio-lation in the derivation.C:::C1; (g : Ct t1 t2)l1 ; (i : CtMt01 t02)L1l1 62 L1Trans1 C1; (g : Ct t1 t2)l1 ; (j : CtM t2t02)fl1g[L1 ;t1 =t01(1):::C2; (g : Ct t1 t2)l1 ; (k : CtM t001 t002)L2l1 2 L2 (2)Trans1 C2; (g : Ct t1 t2)l1 ; (n : CtM t2 t002)L2 ;t1 = t001:::DW.l.o.g., in the derivation steps between (1) and (2) we onlyapply CHRs on (j : CtM t2t02)fl1g[L1 or its su essors,i.e. those resulting from (Trans1) and (Arrow) rules.First, we show that only (Trans1) or (Id) rules ould havebeen applied on (j : CtM t2t02)fl1g[L1 or its su essors.Assume the ontrary, that is some (Pair) (or a similar type-onstru tor) rule has been applied on (j : CtM t2t02)fl1g[L1 .Then, :::; (g : Ct t1 t2)l1 ; t2 = (t3; t4);t02 = (t5; t6);(j : CtM t2t02)fl1g[L1Pair :::; (g : Ct t1 t2)l1 ; t2 = (t3; t4);t02 = (t5; t6);(j1 : CtM t3 t5)fl1g[L1 ; (j2 : CtM t4 t6)fl1g[L1However, then we obtain a y le among types. E.g., assumethat (j1 : CtM t3 t5)fl1g[L1 equals (k : CtM t001 t002)L2 . Wend that t1 =t01; t2 = (t3; t4); t002 = (t5; t6); t001 = t3; t1 = t001whi h implies (g : Ct t1 (t1; t4))l1 . Thus, we obtain a on-tradi tion. Note that by assumption the type equations re-sulting from Ct onstraints (Ct a b yields a = b) must besatis able. Otherwise, the GRDT de nition is invalid.Hen e, we only nd (Trans1) or (Id) appli ations in between(1) and (2). E e tively, we generate a ast fun tion to on-vert t1 into some b whi h then we onvert ba k into t1. How-ever, any su h transformation yields a ast fun tion whi his equivalent to the identity. See Lemma 14. Hen e, thesteps between (1) and (2) are redundant. Hen e, we obtaina shorter derivation.Lemma 16 CHRs are terminating under the terminationondition.17 Proof. Follows immediately. Note that we disallow Ctassumptions of the form g : Ct a (a; b). Hen e, any non-terminating derivation must violate the termination ondi-tion.

برای دانلود متن کامل این مقاله و بیش از 32 میلیون مقاله دیگر ابتدا ثبت نام کنید

ثبت نام

اگر عضو سایت هستید لطفا وارد حساب کاربری خود شوید

منابع مشابه

Constraint-Based Type Inference for Guarded Algebraic Data Types

Guarded algebraic data types subsume the concepts known in the literature as indexed types, guarded recursive datatype constructors, and first-class phantom types, and are closely related to inductive types. They have the distinguishing feature that, when typechecking a function defined by cases, every branch may be checked under different typing assumptions. This mechanism allows exploiting th...

متن کامل

First Steps in Synthetic Guarded Domain Theory

We present the topos S of trees as a model of guarded recursion. We study the internal dependently-typed higher-order logic of S and show that S models two modal operators, on predicates and types, which serve as guards in recursive definitions of terms, predicates, and types. In particular, we show how to solve recursive type equations involving dependent types. We propose that the internal lo...

متن کامل

Type Inference for Guarded Recursive Data Types

We consider type inference for guarded recursive data types (GRDTs) – a recent generalization of algebraic data types. We reduce type inference for GRDTs to unification under a mixed prefix. Thus, we obtain efficient type inference. Inference is incomplete because the set of type constraints allowed to appear in the type system is only a subset of those type constraints generated by type infere...

متن کامل

The Guarded Lambda-Calculus: Programming and Reasoning with Guarded Recursion for Coinductive Types

We present the guarded lambda-calculus, an extension of the simply typed lambda-calculus with guarded recursive and coinductive types. The use of guarded recursive types ensures the productivity of well-typed programs. Guarded recursive types may be transformed into coinductive types by a type-former inspired by modal logic and Atkey-McBride clock quantification, allowing the typing of acausal ...

متن کامل

Guarded Dependent Type Theory with Coinductive Types

We present guarded dependent type theory, gDTT, an extensional dependent type theory with a ‘later’ modality and clock quantifiers for programming and proving with guarded recursive and coinductive types. The later modality is used to ensure the productivity of recursive definitions in a modular, type based, way. Clock quantifiers are used for controlled elimination of the later modality and fo...

متن کامل

The Clocks Are Ticking: No More Delays! Reduction Semantics for Type Theory with Guarded Recursion

Guarded recursion in the sense of Nakano allows general recursive types and terms to be added to type theory without breaking consistency. Recent work has demonstrated applications of guarded recursion such as programming with codata, reasoning about coinductive types, as well as constructing and reasoning about denotational models of general recursive types. Guarded recursion can also be used ...

متن کامل

ذخیره در منابع من


  با ذخیره ی این منبع در منابع من، دسترسی به آن را برای استفاده های بعدی آسان تر کنید

برای دانلود متن کامل این مقاله و بیش از 32 میلیون مقاله دیگر ابتدا ثبت نام کنید

ثبت نام

اگر عضو سایت هستید لطفا وارد حساب کاربری خود شوید

عنوان ژورنال:

دوره   شماره 

صفحات  -

تاریخ انتشار 2008